ResampleFloatCell Subroutine

private subroutine ResampleFloatCell(grid, resampledGrid, newCellsize)

Create a new grid_real with cellsize different from input grid The content of the created grid is filled in with nearest neighbor method

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid
type(grid_real), intent(out) :: resampledGrid
real(kind=float), intent(in) :: newCellsize

Variables

Type Visibility Attributes Name Initial
integer, public :: i
integer, public :: iold
integer, public :: j
integer, public :: jold
real, public :: x
real, public :: y

Source Code

SUBROUTINE ResampleFloatCell &
!
(grid, resampledGrid, newCellsize)


IMPLICIT NONE

! Arguments with intent(in):
TYPE (grid_real), INTENT(IN) :: grid
REAL (KIND = float), INTENT(IN) :: newCellsize

!Arguments with intent(out):
TYPE (grid_real), INTENT(OUT) :: resampledGrid

!Local declarations:
REAL :: x, y
INTEGER :: i, j, iold, jold
!---------------------------end of declarations--------------------------------

!compute number of rows and columns of the resampled grid
resampledGrid % idim = INT(grid%cellsize * grid%idim / newCellsize) + 1
resampledGrid % jdim = INT(grid%cellsize * grid%jdim / newCellsize) + 1

!assign spatial information
resampledGrid % cellsize = newCellsize
resampledGrid % xllcorner = grid % xllcorner
resampledGrid % yllcorner = grid % yllcorner

!allocate resampled grid
ALLOCATE ( resampledGrid % mat (resampledGrid%idim, resampledGrid%jdim))

!copy information from grid to resampled grid
resampledGrid % standard_name = grid % standard_name
resampledGrid % long_name = grid % long_name
resampledGrid % units = grid % units
resampledGrid % varying_mode = grid % varying_mode
resampledGrid % nodata = grid % nodata
resampledGrid % valid_min = grid % valid_min
resampledGrid % valid_max = grid % valid_max
resampledGrid % reference_time = grid % reference_time
resampledGrid % current_time = grid % current_time
resampledGrid % time_index = grid % time_index
resampledGrid % time_unit = grid % time_unit
resampledGrid % esri_pe_string = grid % esri_pe_string
resampledGrid % grid_mapping = grid % grid_mapping


!fill in resampled grid
DO i = 1, resampledGrid % idim
  DO j = 1, resampledGrid % jdim
    CALL GetXY (i, j, resampledGrid, x, y)
    CALL GetIJ (x, y, grid, iold, jold)
    IF (iold > 0 .AND. jold > 0 .AND. iold <= grid % idim .AND. jold <= grid % jdim) THEN
        resampledGrid % mat (i,j) = grid % mat (iold, jold)
    ELSE
        resampledGrid % mat (i,j) = resampledGrid % nodata
    END IF
  END DO
END DO


END SUBROUTINE ResampleFloatCell